home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
4.1
/
OrderedDictionary.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
20KB
|
616 lines
" NAME OrderedDictionary
AUTHOR Ifor Wyn Williams <ifor@uk.ac.man.cs>, ported to 4.1 by Mario Wolczko <mario@cs.man.ac.uk>
CONTRIBUTOR Ifor Wyn Williams <ifor@uk.ac.man.cs>
FUNCTION An ordered dictionary
ST-VERSIONS 4.1
PREREQUISITES
CONFLICTS
DISTRIBUTION global
VERSION 1.3
DATE 26 Nov 1992
SUMMARY A dictionary that behaves like a SequenceableCollection
(except that associations cannot be removed).
"!
'From Objectworks\Smalltalk(R), Release 4.1 of 15 April 1992 on 7 November 1992 at 3:34:49 pm'!
Dictionary variableSubclass: #OrderedDictionary
instanceVariableNames: 'order '
classVariableNames: ''
poolDictionaries: ''
category: 'Collections-Sequenceable'!
OrderedDictionary comment:
'I am a subclass of Dictionary whose elements (associations) are ordered in a similar fashion to OrderedCollection.
I have one instance variable:
order <OrderedCollection> OrderedCollection of keys reflecting the order of associations in the dictionary. '!
!OrderedDictionary methodsFor: 'accessing'!
after: anAssociation
"Return the association after anAssociation in the order. If anAssociation is the
last association in the order, return nil. If anAssociation is
not found, signal an error."
1 to: order size - 1 do: [:index |
(self associationAt: (order at: index)) = anAssociation
ifTrue: [^self associationAt: (order at: index + 1)]].
(self associationAt: (order last)) = anAssociation
ifTrue: [^nil]
ifFalse: [^self keyNotFoundError: anAssociation key]!
associations
"Answer an OrderedCollection containing the receiver's associations."
| anOrderedCollection |
anOrderedCollection := OrderedCollection new: order size.
order do: [:key | anOrderedCollection add: (self associationAt: key)].
^anOrderedCollection!
at: key put: anObject
"Set the value at key to be anObject. If key is not found, create a new
entry for key and set its value to anObject. Answer anObject."
(order includes: key)
ifFalse: [order add: key].
^super at: key put: anObject!
atAll: anInterval put: anObject
"Put anObject into the value field of every association specified by the interval."
anInterval do: [:index | self at: (order at: index) put: anObject]!
atAllPut: anObject
"Put anObject into the value field of every association in the dictionary."
order do: [:key | self at: key put: anObject]!
before: anAssociation
"Return the association before anAssociation in the order. If anAssociation is the
first association in the order, return the undefined object. If anAssociation is
not found, invoke an error notifier"
2 to: order size do: [:index |
(self associationAt: (order at: index)) = anAssociation
ifTrue: [^self associationAt: (order at: index - 1)]].
(self associationAt: order first) = anAssociation
ifTrue: [^nil]
ifFalse: [^self keyNotFoundError: anAssociation key]!
first
"Answer the first association of the receiver. Provide an error
notification if the receiver contains no elements."
order emptyCheck.
^self associationAt: (order first)!
keys
"Answer a OrderedCollection containing the receiver's keys."
^order copy!
last
"Answer the last association of the receiver. Provide an error
notification if the receiver contains no elements."
order emptyCheck.
^self associationAt: (order last)!
order
^order!
values
"Answer a OrderedCollection containing the receiver's values."
| anOrderedCollection |
anOrderedCollection := OrderedCollection new: order size.
order do: [:key | anOrderedCollection add: (self at: key)].
^anOrderedCollection! !
!OrderedDictionary methodsFor: 'testing'!
occurrencesOfKey: aKey
"Answer how many of the dictionary's keys are equal to aKey."
| count |
count := 0.
1 to: self size do: [:index | aKey = (order at: index) ifTrue: [count := count + 1]].
^count!
occurrencesOfValue: aValue
"Answer how many of the dictionary's values are equal to aValue."
| count |
count := 0.
1 to: self size do: [:index | aValue = (self at: (order at: index)) ifTrue: [count := count + 1]].
^count! !
!OrderedDictionary methodsFor: 'adding'!
add: anAssociation
"Add anAssociation to the dictionary."
| key |
key := anAssociation key.
(super includesKey: key)
ifFalse: [order add: key].
^super add: anAssociation!
add: anAssociation after: oldAssociation
"Add the argument, anAssociation, as an element of the dictionary.
Put it in the position just after oldAssociation. Answer anAssociation."
| index |
index := self indexOfAssociation: oldAssociation ifAbsent: [self keyNotFoundError: oldAssociation key].
self removeFromOrder: anAssociation key.
order add: anAssociation key after: (order at: index).
super add: anAssociation.
^anAssociation!
add: anAssociation before: oldAssociation
"Add the argument, anAssociation, as an element of the dictionary. Put it
in the position just before oldAssociation. Answer anAssociation."
| index |
index := self indexOfAssociation: oldAssociation ifAbsent: [self keyNotFoundError: oldAssociation key].
self removeFromOrder: anAssociation key.
order add: anAssociation key before: (order at: index).
super add: anAssociation.
^anAssociation!
add: anAssociation beforeIndex: spot
"Add the argument, anAssociation, as an element of the receiver. Put it
in the position just before the indexed position spot. Answer anAssociation."
self removeFromOrder: anAssociation key.
order add: anAssociation key beforeIndex: spot.
^super add: anAssociation!
addAll: aCollectionOfAssociations
"Add each element of aCollectionOfAssociations at my end."
(aCollectionOfAssociations respondsTo: #associationsDo:)
ifTrue: [aCollectionOfAssociations associationsDo: [:elems | self add: elems]]
ifFalse: [aCollectionOfAssociations do: [:elems | self add: elems]].
^aCollectionOfAssociations!
addAllFirst: anOrderedCollectionOfAssociations
"Add each element of anOrderedCollectionOfAssociations at the beginning of the receiver."
anOrderedCollectionOfAssociations reverseDo: [:each | self addFirst: each].
^anOrderedCollectionOfAssociations!
addAllLast: anOrderedCollectionOfAssociations
"Add each element of anOrderedCollectionOfAssociations at the end of the receiver."
anOrderedCollectionOfAssociations do: [:each | self addLast: each].
^anOrderedCollectionOfAssociations!
addFirst: anAssociation
"Add anAssociation to the beginning of the receiver. Answer anAssociation."
self removeFromOrder: anAssociation key.
order addFirst: anAssociation key.
^super add: anAssociation.!
addLast: anAssociation
"Add anAssociation to the end of the receiver. Answer anAssociation."
self removeFromOrder: anAssociation key.
order addLast: anAssociation key.
^super add: anAssociation.!
grow
"Increase the number of elements in the dictionary"
| newSelf |
newSelf := (self class) new: (self basicSize + self growSize).
order do: [:key | newSelf add: (self associationAt: key)].
self become: newSelf! !
!OrderedDictionary methodsFor: 'copying'!
copyEmpty
"Answer a copy of the receiver that contains no elements."
^(self class) new: 10!
copyEmpty: aSize
"Answer a copy of the receiver that contains no elements."
^(self class) new: aSize!
copyFrom: startIndex to: endIndex
"Answer a copy of the receiver that contains elements from
position startIndex to endIndex."
| newDict |
endIndex < startIndex ifTrue: [^self copyEmpty].
(startIndex < 1 or: [endIndex > order size])
ifTrue: [^self error: 'Index out of bounds'].
newDict := self copyEmpty: endIndex - startIndex + 1.
startIndex to: endIndex do: [:index | newDict add: (self associationAt: (order at: index))].
^newDict!
copyWith: anAssociation
"Answer a copy of the dictionary that is 1 bigger than the receiver and
includes the argument, anAssociation, at the end."
| newDict |
newDict := self copy.
newDict add: anAssociation.
^newDict!
copyWithout: anAssociation
"Answer a copy of the dictionary that is 1 smaller than the receiver and does
not includes the argument, anAssociation"
| newDict |
newDict := OrderedDictionary new: order size - 1.
self associationsDo: [:assoc | anAssociation = assoc ifFalse: [newDict add: assoc]]! !
!OrderedDictionary methodsFor: 'dictionary removing'!
removeAssociation: anAssociation ifAbsent: anExceptionBlock
"Remove the key and value association, anAssociation, from the
receiver. If not found, answer the result of evaluating
anExceptionBlock, otherwise answer anAssociation."
self removeFromOrder: anAssociation key.
^super removeAssociation: anAssociation ifAbsent: anExceptionBlock!
removeKey: key ifAbsent: aBlock
"Remove key from the receiver. If key is not in the receiver,
answer the result of evaluating aBlock. Otherwise, answer the value
associated with key."
self removeFromOrder: key.
^super removeKey: key ifAbsent: aBlock! !
!OrderedDictionary methodsFor: 'enumerating'!
associationsDo: aBlock
"Evaluate aBlock for each of the dictionary's associations."
order do: [:key | aBlock value: (self associationAt: key)]!
associationsDo: aBlock from: firstIndex to: secondIndex
"Evaluate aBlock with each of the dictionary's associations from index
firstIndex to index secondIndex as the argument."
firstIndex to: secondIndex do: [:index | aBlock value: (self associationAt: (order at: index))]!
collect: aBlock
"Evaluate aBlock with each of the associations of the dictionary as the
argument. The block should return an association which will be added to the
new OrderedDictionary"
| newDict |
newDict := OrderedDictionary new.
1 to: order size do: [:index | newDict add: (aBlock value: (self associationAt: (order at: index)))].
^newDict!
do: aBlock
"Evaluate aBlock for each of the dictionary's values."
order do: [:key | aBlock value: (self at: key)]!
do: aBlock from: firstIndex to: secondIndex
"Evaluate aBlock with each of the dictionary's associations from index
firstIndex to index secondIndex as the argument."
firstIndex to: secondIndex do: [:index | aBlock value: (self at: (order at: index))]!
findFirst: aBlock
"Answer the index of the first association in the dictionary for which aBlock
evaluates to true. If the block never evaluates to true, return 0"
1 to: order size do: [:index |
(aBlock value: (self associationAt: (order at: index)))
ifTrue: [^index]].
^0!
findLast: aBlock
"Evaluate aBlock for the each of the associations in reverse order. Return the index
of the first that evaluates to true. If the block never evaluates to true, return 0"
order size
to: 1
by: -1
do: [:index |
(aBlock value: (self associationAt: (order at: index)))
ifTrue: [^index]].
^0!
reverse
"Answer with a new OrderedDictionary with its associations in reverse order."
| newDict|
newDict := OrderedDictionary new.
order size
to: 1
by: -1
do:
[:index || key |
key := order at: index.
newDict at: key put: (self at: key)].
^newDict!
reverseDo: aBlock
"Evaluate aBlock with each of the dictionary's associations as the argument,
starting with the last element and taking each in sequence up to the first."
order size
to: 1
by: -1
do: [:index | aBlock value: (self associationAt: (order at: index))]!
select: aBlock
"Evaluate aBlock with each of the dictionary's associations as the argument.
Collect into a new OrderedDictionary only those associations for which
aBlock evaluates to true. Answer the new OrderedDictionary."
| newDict |
newDict := OrderedDictionary new.
1 to: order size do:
[:index || key |
key := order at: index.
(aBlock value: (self associationAt: key))
ifTrue: [newDict add: (self associationAt: key)]].
^newDict! !
!OrderedDictionary methodsFor: 'accessing index'!
identityIndexOfAssociation: anAssociation
"Answer the identity index of anAssociation within the receiver. If the receiver
does not contain anAssociation, answer 0."
^self identityIndexOfAssociation: anAssociation ifAbsent: [0]!
identityIndexOfAssociation: anAssociation ifAbsent: exceptionBlock
"Answer the identity index of anAssociation within the receiver. If the receiver
does not contain anAssociation, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(self associationAt: (order at: i)) == anAssociation ifTrue: [^i]].
^exceptionBlock value!
identityIndexOfKey: aKey
"Answer the identity index of aKey within the receiver. If the receiver
does not contain aKey, answer 0."
^self identityIndexOfKey: aKey ifAbsent: [0]!
identityIndexOfKey: aKey ifAbsent: exceptionBlock
"Answer the identity index of aKey within the receiver. If the receiver does
not contain aKey, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(order at: i) == aKey ifTrue: [^i]].
^exceptionBlock value!
identityIndexOfValue: aValue
"Answer the identity index of aValue within the receiver. If the receiver
does not contain aValue, answer 0."
^self identityIndexOfValue: aValue ifAbsent: [0]!
identityIndexOfValue: aValue ifAbsent: exceptionBlock
"Answer the identity index of aValue within the receiver. If the receiver
does not contain aValue, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(self at: (order at: i)) == aValue ifTrue: [^i]].
^exceptionBlock value!
indexOfAssociation: anAssociation
"Answer the index of anAssociation within the receiver. If the receiver does
not contain anAssociation, answer 0."
^self indexOfAssociation: anAssociation ifAbsent: [0]!
indexOfAssociation: anAssociation ifAbsent: exceptionBlock
"Answer the identity index of anAssociation within the receiver. If the receiver
does not contain anAssociation, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(self associationAt: (order at: i)) = anAssociation ifTrue: [^i]].
^exceptionBlock value!
indexOfKey: aKey
"Answer the index of aKey within the receiver. If the receiver does
not contain aKey, answer 0."
^self indexOfKey: aKey ifAbsent: [0]!
indexOfKey: aKey ifAbsent: exceptionBlock
"Answer the identity index of aKey within the receiver. If the receiver does
not contain aKey, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(order at: i) = aKey ifTrue: [^i]].
^exceptionBlock value!
indexOfValue: aValue
"Answer the index of aValue within the receiver. If the receiver does
not contain aValue, answer 0."
^self indexOfValue: aValue ifAbsent: [0]!
indexOfValue: aValue ifAbsent: exceptionBlock
"Answer the identity index of aValue within the receiver. If the receiver
does not contain aValue, answer the result of evaluating the exceptionBlock."
1 to: order size do: [:i |
(self at: (order at: i)) = aValue ifTrue: [^i]].
^exceptionBlock value!
nextIndexOfAssociation: aAssociation from: startIndex to: stopIndex
"Answer the next index of aAssociation within the receiver between startIndex
and stopIndex. If the receiver does not contain aAssociation, answer nil"
startIndex to: stopIndex do: [:i |
(self associationAt: (order at: i)) = aAssociation ifTrue: [^i]].
^nil!
nextIndexOfKey: aKey from: startIndex to: stopIndex
"Answer the next index of aKey within the receiver between startIndex and
stopIndex. If the receiver does not contain aKey, answer nil"
startIndex to: stopIndex do: [:i |
(order at: i) = aKey ifTrue: [^i]].
^nil!
nextIndexOfValue: aValue from: startIndex to: stopIndex
"Answer the next index of aValue within the receiver between startIndex and
stopIndex. If the receiver does not contain aValue, answer nil"
startIndex to: stopIndex do: [:i |
(self at: (order at: i)) = aValue ifTrue: [^i]].
^nil!
prevIndexOfAssociation: aAssociation from: startIndex to: stopIndex
"Answer the previous index of aAssociation within the receiver between startIndex
and stopIndex working backwards through the receiver. If the receiver does
not contain aAssociation, answer nil"
startIndex
to: stopIndex
by: -1
do: [:i |
(self associationAt: (order at: i)) = aAssociation ifTrue: [^i]].
^nil!
prevIndexOfKey: aKey from: startIndex to: stopIndex
"Answer the previous index of aKey within the receiver between startIndex and
stopIndex working backwards through the receiver. If the receiver does not
contain aKey, answer nil"
startIndex
to: stopIndex
by: -1
do: [:i | (order at: i) = aKey ifTrue: [^i]].
^nil!
prevIndexOfValue: aValue from: startIndex to: stopIndex
"Answer the previous index of aValue within the receiver between startIndex
and stopIndex working backwards through the receiver. If the receiver does
not contain aValue, answer nil"
startIndex
to: stopIndex
by: -1
do: [:i | (self at: (order at: i)) = aValue ifTrue: [^i]].
^nil! !
!OrderedDictionary methodsFor: 'user interface'!
inspect
"Create and schedule a DictionaryInspector in which the user can examine the
receiver's variables."
Cursor wait showWhile: [Inspector open: (OrderedDictionaryInspector inspect: self)]! !
!OrderedDictionary methodsFor: 'private'!
initialize
order := OrderedCollection new!
removeFromOrder: aKey
order remove: aKey ifAbsent: []! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
OrderedDictionary class
instanceVariableNames: ''!
!OrderedDictionary class methodsFor: 'test'!
test1
"OrderedDictionary test1"
| selectTest o3 o5 a1 a2 a3 a4 a6 d1 col1 col2 col3 d2 b1 b2 b3 b4 b5 c1 c2 c3 c4 c5 e1 e2 e3 e4 e5 |
d1 := OrderedDictionary new.
d1 at: 1 put: 'one'.
d1 at: 2 put: 'two'.
d1 at: 3 put: 'three'.
d1 at: 4 put: 'four'.
d1 at: 5 put: 'five'.
d1 at: 6 put: 'six'.
d1 at: 7 put: 'seven'.
d2 := OrderedDictionary new.
d2 at: 11 put: 'eleven'.
d2 at: 12 put: 'twelve'.
d2 at: 13 put: 'thirteen'.
d2 at: 14 put: 'fourteen'.
d2 at: 15 put: 'fifteen'.
d2 at: 16 put: 'sixteen'.
d2 at: 17 put: 'seventeen'.
b1 := Association key: 31 value: 'threeOne'.
b2 := Association key: 32 value: 'threeTwo'.
b3 := Association key: 33 value: 'threeThree'.
b4 := Association key: 34 value: 'threeFour'.
b5 := Association key: 35 value: 'threeFive'.
c1 := Association key: 41 value: 'fourOne'.
c2 := Association key: 42 value: 'fourTwo'.
c3 := Association key: 43 value: 'fourThree'.
c4 := Association key: 44 value: 'fourFour'.
c5 := Association key: 45 value: 'fourFive'.
e1 := Association key: 51 value: 'fiveOne'.
e2 := Association key: 52 value: 'fiveTwo'.
e3 := Association key: 53 value: 'fiveThree'.
e4 := Association key: 54 value: 'fiveFour'.
e5 := Association key: 55 value: 'fiveFive'.
col1 := OrderedCollection new.
col1 add: b1; add: b2; add: b3; add: b4; add: b5.
col2 := OrderedCollection new.
col2 add: c1; add: c2; add: c3; add: c4; add: c5.
col3 := OrderedCollection new.
col3 add: e1; add: e2; add: e3; add: e4; add: e5.
o3 := Association key: 3 value: 'three'.
o5 := Association key: 5 value: 'five'.
a1 := Association key: 21 value: 'twentyOne'.
a2 := Association key: 22 value: 'twentyTwo'.
a3 := Association key: 23 value: 'twentyThree'.
a4 := Association key: 24 value: 'twentyFour'.
a6 := Association key: 21 value: 'twentyOneTwice'.
d1 add: a1 after: o3.
d1 add: a2 after: o5.
d1 add: a3 before: a2.
d1 add: a4 beforeIndex: 4.
d1 add: a6 beforeIndex: 4.
d1 addAll: col1.
d1 addAllFirst: col2 .
d1 addAllLast: col3.
"collectTest := d1 collect: [:assoc| Association key: (assoc key) value: 42]."
selectTest:= d1 select: [:assoc| (assoc key) > 20 ].
selectTest := selectTest reverse.
(d1 atAll: (Interval from: 5 to: 10) put: 42 ).
(d1 copyWithout: a6 ) inspect
" OrderedDictionary (41->'fourOne' 42->'fourTwo' 43->'fourThree' 44->'fourFour' 45->42 1->42 2->42 3->42 21->42 24->42 4->'four' 5->'five' 23->'twentyThree' 22->'twentyTwo' 6->'six' 7->'seven' 31->'threeOne' 32->'threeTwo' 33->'threeThree' 34->'threeFour' 35->'threeFive' 51->'fiveOne' 52->'fiveTwo' 53->'fiveThree' 54->'fiveFour' 55->'fiveFive' )"! !
!OrderedDictionary class methodsFor: 'instance creation'!
new
^super new initialize!
new: anInteger
^(super new: anInteger) initialize! !
DictionaryInspector subclass: #OrderedDictionaryInspector
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Tools-Inspector'!
!OrderedDictionaryInspector methodsFor: 'field list'!
fieldList
"Answer a collection of the keys of the inspected dictionary."
^object order! !